home *** CD-ROM | disk | FTP | other *** search
/ Hardcore Visual Basic 5.0 (2nd Edition) / Hardcore Visual Basic 5.0 - Second Edition (1997)(Microsoft Press).iso / Code / modtool.cls < prev    next >
Text File  |  1997-06-14  |  24KB  |  653 lines

  1. VERSION 1.0 CLASS
  2. BEGIN
  3.   MultiUse = -1  'True
  4. END
  5. Attribute VB_Name = "GModTool"
  6. Attribute VB_GlobalNameSpace = True
  7. Attribute VB_Creatable = True
  8. Attribute VB_PredeclaredId = False
  9. Attribute VB_Exposed = True
  10. Option Explicit
  11.  
  12. '$ Uses UTILITY.BAS DEBUG.BAS WINTOOL.BAS
  13.  
  14. '' ToolHelp functions for Windows 95 and Windows NT
  15.  
  16. ' Windows 95 Private Declares, constants, and Private Types
  17. ' Use the ToolHelp functions found in KERNEL32.DLL
  18.  
  19. Public Enum EErrorModTool
  20.     eeBaseModTool = 13530   ' ModTool
  21. End Enum
  22.  
  23. Const MAX_MODULE_NAME32 = 255
  24.  
  25. ' ****** Shapshot function *****
  26.  
  27. Private Declare Function CreateToolhelp32Snapshot Lib "KERNEL32" ( _
  28.     ByVal dwFlags As Long, ByVal th32ProcessID As Long) As Long
  29.  
  30. '
  31. ' The th32ProcessID argument is only used if TH32CS_SNAPHEAPLIST or
  32. ' TH32CS_SNAPMODULE is specified. th32ProcessID == 0 means the current
  33. ' process.
  34. '
  35. ' NOTE that all of the snapshots are global except for the heap and module
  36. '       lists which are process specific. To enumerate the heap or module
  37. '       state for all WIN32 processes call with TH32CS_SNAPALL and the
  38. '       current process. Then for each process in the TH32CS_SNAPPROCESS
  39. '       list that isn't the current process, do a call with just
  40. '       TH32CS_SNAPHEAPLIST and/or TH32CS_SNAPMODULE.
  41. '
  42. ' dwFlags
  43. '
  44. Const TH32CS_SNAPHEAPLIST = &H1&
  45. Const TH32CS_SNAPPROCESS = &H2&
  46. Const TH32CS_SNAPTHREAD = &H4&
  47. Const TH32CS_SNAPMODULE = &H8&
  48. Const TH32CS_SNAPALL = (TH32CS_SNAPHEAPLIST Or TH32CS_SNAPPROCESS Or _
  49.                         TH32CS_SNAPTHREAD Or TH32CS_SNAPMODULE)
  50. Const TH32CS_INHERIT = &H80000000
  51. '
  52. ' Use CloseHandle to destroy the snapshot
  53. '
  54.  
  55. ' ****** heap walking ******
  56. #If 0 Then  ' In Visual Basic? No way!
  57.  
  58. Private Type HEAPLIST32
  59.     dwSize As Long
  60.     th32ProcessID As Long    ' owning process
  61.     th32HeapID As Long       ' heap (in owning process's context!)
  62.     dwFlags As Long
  63. End Type
  64.  
  65. '
  66. ' dwFlags
  67. '
  68. Const HF32_DEFAULT = 1        ' process's default heap
  69. Const HF32_SHARED = 2         ' is shared heap
  70.  
  71. Private Declare Function Heap32ListFirst Lib "TOOLHELP32" ( _
  72.     ByVal hSnapshot As Long, lphl As HEAPLIST32) As Long
  73. Private Declare Function Heap32ListNext Lib "TOOLHELP32" ( _
  74.     ByVal hSnapshot As Long, lphl As HEAPLIST32) As Long
  75.  
  76. Private Type HEAPENTRY32
  77.     dwSize As Long
  78.     hHandle As Long         ' Handle of this heap block
  79.     dwAddress As Long       ' Linear address of start of block
  80.     dwBlockSize As Long     ' Size of block in bytes
  81.     dwFlags As Long
  82.     dwLockCount As Long
  83.     dwResvd As Long
  84.     th32ProcessID As Long   ' Owning process
  85.     th32HeapID As Long      ' Heap block is in
  86. End Type
  87.  
  88. '
  89. ' dwFlags
  90. '
  91. Const LF32_FIXED = &H1&
  92. Const LF32_FREE = &H2&
  93. Const LF32_MOVEABLE = &H4&
  94.  
  95. Private Declare Function Heap32First Lib "KERNEL32" (lphe As HEAPENTRY32, _
  96.     ByVal th32ProcessID As Long, ByVal th32HeapID As Long) As Long
  97. Private Declare Function Heap32Next Lib "KERNEL32" (lphe As HEAPENTRY32) As Long
  98. Private Declare Function Toolhelp32ReadProcessMemory Lib "KERNEL32" ( _
  99.     ByVal th32ProcessID As Long, ByVal lpBaseAddress As Long, _
  100.     ByVal lpBuffer As Long, ByVal cbRead As Long, _
  101.     lpNumberOfBytesRead As Long) As Long
  102. #End If
  103.  
  104. ' ***** Process walking ****
  105.  
  106. Private Type PROCESSENTRY32
  107.     dwSize As Long
  108.     cntUsage As Long
  109.     th32ProcessID As Long           ' This process
  110.     th32DefaultHeapID As Long
  111.     th32ModuleID As Long            ' Associated exe
  112.     cntThreads As Long
  113.     th32ParentProcessID As Long     ' This process's parent process
  114.     pcPriClassBase As Long          ' Base priority of process's threads
  115.     dwFlags As Long
  116.     szExeFile As String * 260       ' MAX_PATH
  117. End Type
  118.  
  119. Private Declare Function Process32First Lib "KERNEL32" ( _
  120.     ByVal hSnapshot As Long, lppe As PROCESSENTRY32) As Long
  121. Private Declare Function Process32Next Lib "KERNEL32" ( _
  122.     ByVal hSnapshot As Long, lppe As PROCESSENTRY32) As Long
  123.  
  124. ' ***** Thread walking *****
  125. #If 0 Then          ' Don't bother!
  126. Private Type THREADENTRY32
  127.     dwSize As Long
  128.     cntUsage As Long
  129.     th32ThreadID As Long        ' this thread
  130.     th32OwnerProcessID As Long  ' Process this thread is associated with
  131.     tpBasePri As Long
  132.     tpDeltaPri As Long
  133.     dwFlags As Long
  134. End Type
  135.  
  136. Private Declare Function Thread32First Lib "KERNEL32" ( _
  137.     ByVal hSnapshot As Long, lpte As THREADENTRY32) As Long
  138. Private Declare Function Thread32Next Lib "KERNEL32" ( _
  139.     ByVal hSnapshot As Long, lpte As THREADENTRY32) As Long
  140. #End If
  141.  
  142. ' ***** Module walking *****
  143.  
  144. Private Type MODULEENTRY32
  145.     dwSize As Long
  146.     th32ModuleID As Long        ' This module
  147.     th32ProcessID As Long       ' owning process
  148.     GlblcntUsage As Long        ' Global usage count on the module
  149.     ProccntUsage As Long        ' Module usage count in th32ProcessID's context
  150.     modBaseAddr As Long         ' Base address of module in th32ProcessID's context
  151.     modBaseSize As Long         ' Size in bytes of module starting at modBaseAddr
  152.     hModule As Long             ' The hModule of this module in th32ProcessID's context
  153.     szModule As String * 256    ' MAX_MODULE_NAME32 + 1
  154.     szExePath As String * 260   ' MAX_PATH
  155. End Type
  156.  
  157. '
  158. ' NOTE CAREFULLY that the modBaseAddr and hModule fields are valid ONLY
  159. ' in th32ProcessID's process context.
  160. '
  161.  
  162. Private Declare Function Module32First Lib "KERNEL32" ( _
  163.     ByVal hSnapshot As Long, lpme As MODULEENTRY32) As Long
  164. Private Declare Function Module32Next Lib "KERNEL32" ( _
  165.     ByVal hSnapshot As Long, lpme As MODULEENTRY32) As Long
  166.     
  167.  
  168. ' Windows NT Private Declares, constants, and Private Types
  169. ' Use the PSAPI functions found in PSAPI.DLL
  170.     
  171. Private Declare Function EnumProcesses Lib "PSAPI" ( _
  172.     lpidProcess As Long, ByVal cb As Long, cbNeeded As Long) As Long
  173.  
  174. Private Declare Function EnumProcessModules Lib "PSAPI" ( _
  175.     ByVal hProcess As Long, lphModule As Long, _
  176.     ByVal cb As Long, lpcbNeeded As Long) As Long
  177.  
  178. Private Declare Function GetModuleBaseName Lib "PSAPI" Alias "GetModuleBaseNameA" ( _
  179.     ByVal hProcess As Long, ByVal hModule As Long, _
  180.     ByVal lpBaseName As String, ByVal nSize As Long) As Long
  181.  
  182. Private Declare Function GetModuleBaseNameW Lib "PSAPI" ( _
  183.     ByVal hProcess As Long, ByVal hModule As Long, _
  184.     lpBaseName As Byte, ByVal nSize As Long) As Long
  185.  
  186. Private Declare Function GetModuleFileNameEx Lib "PSAPI" Alias "GetModuleFileNameExA" ( _
  187.     ByVal hProcess As Long, ByVal hModule As Long, _
  188.     ByVal lpFileName As String, ByVal nSize As Long) As Long
  189.  
  190. Private Declare Function GetModuleFileNameExW Lib "PSAPI" ( _
  191.     ByVal hProcess As Long, ByVal hModule As Long, _
  192.     lpFileName As Byte, ByVal nSize As Long) As Long
  193.  
  194. Private Type MODULEINFO
  195.     lpBaseOfDll As Long
  196.     SizeOfImage As Long
  197.     EntryPoint As Long
  198. End Type
  199.  
  200. Private Declare Function GetModuleInformation Lib "PSAPI" ( _
  201.     ByVal hProcess As Long, ByVal hModule As Long, _
  202.     lpmodinfo As MODULEINFO, ByVal cb As Long) As Long
  203.  
  204. ' Additional PSAPI functions that I don't use from Visual Basic
  205. #If 0 Then
  206. Private Declare Function EmptyWorkingSet Lib "PSAPI" ( _
  207.     ByVal hProcess As Long) As Long
  208.  
  209. Private Declare Function QueryWorkingSet Lib "PSAPI" ( _
  210.     ByVal hProcess As Long, ByVal pv As Long, _
  211.     ByVal cb As Long) As Long
  212.  
  213. Private Declare Function InitializeProcessForWsWatch Lib "PSAPI" ( _
  214.     ByVal hProcess As Long) As Long
  215.  
  216. Private Type PSAPI_WS_WATCH_INFORMATION
  217.     FaultingPc As Long
  218.     FaultingVa As Long
  219. End Type
  220.  
  221. Private Declare Function GetWsChanges Lib "PSAPI" ( _
  222.     ByVal hProcess As Long, _
  223.     lpWatchInfo As PSAPI_WS_WATCH_INFORMATION) As Long
  224.  
  225. Private Declare Function GetMappedFileNameA Lib "PSAPI" ( _
  226.     ByVal hProcess As Long, lpv As Long, _
  227.     lpFileName As Byte, ByVal nSize As Long) As Long
  228.  
  229. Private Declare Function GetMappedFileNameW Lib "PSAPI" ( _
  230.     ByVal hProcess As Long, lpv As Long, _
  231.     ByVal lpFileName As String, ByVal nSize As Long) As Long
  232.  
  233. Private Declare Function EnumDeviceDrivers Lib "PSAPI" ( _
  234.     ByVal lpImageBase As Long, ByVal cb As Long, _
  235.     lpcbNeeded As Long) As Long
  236.  
  237. Private Declare Function GetDeviceDriverBaseNameA Lib "PSAPI" ( _
  238.     ByVal lpImageBase As Long, ByVal lpBaseName As String, _
  239.     ByVal nSize As Long) As Long
  240.  
  241. Private Declare Function GetDeviceDriverBaseNameW Lib "PSAPI" ( _
  242.     ByVal lpImageBase As Long, lpBaseName As Byte, _
  243.     ByVal nSize As Long) As Long
  244.  
  245. Private Declare Function GetDeviceDriverFileNameA Lib "PSAPI" ( _
  246.     ByVal lpImageBase As Long, ByVal lpFileName As String, _
  247.     ByVal nSize As Long) As Long
  248.  
  249. Private Declare Function GetDeviceDriverFileNameW Lib "PSAPI" ( _
  250.     ByVal lpImageBase As Long, lpFileName As Byte, _
  251.     ByVal nSize As Long) As Long
  252.  
  253. ' Structure for GetProcessMemoryInfo()
  254.  
  255. Private Type PROCESS_MEMORY_COUNTERS
  256.     cb As Long
  257.     PageFaultCount As Long
  258.     PeakWorkingSetSize As Long
  259.     WorkingSetSize As Long
  260.     QuotaPeakPagedPoolUsage As Long
  261.     QuotaPagedPoolUsage As Long
  262.     QuotaPeakNonPagedPoolUsage As Long
  263.     QuotaNonPagedPoolUsage As Long
  264.     PagefileUsage As Long
  265.     PeakPagefileUsage As Long
  266. End Type
  267.  
  268. Private Declare Function GetProcessMemoryInfo Lib "PSAPI" ( _
  269.     ByVal hProcess As Long, ppsmemCounters As PROCESS_MEMORY_COUNTERS, _
  270.     ByVal cb As Long) As Long
  271. #End If
  272.  
  273. Function CreateProcessList() As CVector
  274.     Dim c As Long, f As Long, sName As String
  275.     Dim vec As CVector, process As CProcess
  276.     Set vec = New CVector
  277.     
  278.     If MUtility.IsNT = False Then
  279.         ' Windows 95 uses ToolHelp32 functions
  280.         Dim hSnap As Long, proc As PROCESSENTRY32
  281.         ' Take a picture of current process list
  282.         hSnap = CreateToolhelp32Snapshot(TH32CS_SNAPPROCESS, 0)
  283.         If hSnap = hNull Then Exit Function
  284.         proc.dwSize = Len(proc)
  285.         ' Iterate through the processes
  286.         f = Process32First(hSnap, proc)
  287.         Do While f
  288.             ' Put this process in vector and count it
  289.             sName = MUtility.StrZToStr(proc.szExeFile)
  290.             Set process = New CProcess
  291.             process.Create proc.th32ProcessID, MUtility.GetFileBaseExt(sName)
  292.             c = c + 1
  293.             Set vec(c) = process
  294.             f = Process32Next(hSnap, proc)
  295.         Loop
  296.     Else
  297.         ' Windows NT uses PSAPI functions
  298.         Dim i As Long, iCur As Long, cRequest As Long, cGot As Long
  299.         Dim aProcesses() As Long, hProcess As Long, hModule As Long
  300.         cRequest = 96       ' Request in bytes for 24 processes
  301.         Do
  302.             ReDim aProcesses(0 To (cRequest / 4) - 1) As Long
  303.             f = EnumProcesses(aProcesses(0), cRequest, cGot)
  304.             If f = 0 Then Exit Function
  305.             If cGot < cRequest Then Exit Do
  306.             cRequest = cRequest * 2
  307.         Loop
  308.         cGot = cGot / 4     ' From bytes to processes
  309.         ReDim Preserve aProcesses(0 To cGot - 1) As Long
  310.         
  311.         For i = 0 To cGot - 1
  312.             hProcess = OpenProcess(PROCESS_QUERY_INFORMATION Or _
  313.                                    PROCESS_VM_READ, 0, _
  314.                                    aProcesses(i))
  315.             ' Ignore processes that fail (probably no
  316.             ' security rights)
  317.             If hProcess = 0 Then GoTo NextFor
  318.             ' Get first module only
  319.             f = EnumProcessModules(hProcess, hModule, 4, c)
  320.             If f = 0 Then GoTo NextFor
  321.             sName = String$(cMaxPath, 0)
  322.             c = GetModuleFileNameEx(hProcess, hModule, sName, cMaxPath)
  323.             ' Put this process in vector and count it
  324.             Set process = New CProcess
  325.             process.Create aProcesses(i), Left$(sName, c)
  326.             iCur = iCur + 1
  327.             Set vec(iCur) = process
  328. NextFor:
  329.         Next
  330.     End If
  331.     Set CreateProcessList = vec
  332. End Function
  333.  
  334. Function CreateModuleList(idProcessA As Long) As CVector
  335.     Dim sName As String, f As Long, c As Long, i As Long, iCur As Long
  336.     Dim vec As CVector, module As CModule
  337.     Set vec = New CVector
  338.     
  339.     If MUtility.IsNT = False Then
  340.         ' Windows 95 uses ToolHelp functions
  341.         Dim modu As MODULEENTRY32, hSnap As Long
  342.         hSnap = CreateToolhelp32Snapshot(TH32CS_SNAPMODULE, idProcessA)
  343.         If hSnap = hNull Then Exit Function
  344.         modu.dwSize = Len(modu)
  345.         f = Module32First(hSnap, modu)
  346.         Do While f
  347.             Set module = New CModule
  348.             sName = MUtility.GetFileBaseExt(MUtility.StrZToStr(modu.szExePath))
  349.             ' Validate module handle
  350.             If sName = ExeNameFromMod(modu.hModule) Then
  351.                 module.Create modu.th32ProcessID, modu.modBaseAddr, sName
  352.                 i = i + 1
  353.                 Set vec(i) = module
  354.             End If
  355.             f = Module32Next(hSnap, modu)
  356.         Loop
  357.     Else
  358.         ' Windows NT uses PSAPI functions
  359.         Dim cRequest As Long, cGot As Long
  360.         Dim aModules() As Long, hProcess As Long, hModule As Long
  361.         ' Get a handle
  362.         hProcess = OpenProcess(PROCESS_QUERY_INFORMATION Or _
  363.                                PROCESS_VM_READ, 0, idProcessA)
  364.         If hProcess = 0 Then Exit Function
  365.         cRequest = 48       ' Request in bytes (16 modules)
  366.         Do
  367.             ReDim aModules(0 To (cRequest / 4) - 1) As Long
  368.             f = EnumProcessModules(hProcess, aModules(0), cRequest, cGot)
  369.             If f = 0 Then Exit Function
  370.             If cGot < cRequest Then Exit Do
  371.             cRequest = cRequest * 2
  372.         Loop
  373.         cGot = cGot / 4     ' From bytes to modules
  374.         ReDim Preserve aModules(0 To cGot - 1) As Long
  375.  
  376.         For i = 0 To cGot - 1
  377.             sName = String$(cMaxPath, 0)
  378.             c = GetModuleFileNameEx(hProcess, aModules(i), sName, cMaxPath)
  379.             If c = 0 Then GoTo NextFor
  380.             sName = Left$(sName, c)
  381.             Set module = New CModule
  382.             module.Create idProcessA, aModules(i), sName
  383.             iCur = iCur + 1
  384.             Set vec(iCur) = module
  385. NextFor:
  386.         Next
  387.     End If
  388.     Set CreateModuleList = vec
  389. End Function
  390.  
  391. Function ExeNameFromMod(ByVal hMod As Long) As String
  392.     Dim sT As String, cT As Long
  393.     cT = 256: sT = String$(256, 0)
  394.     cT = GetModuleFileName(hMod, sT, cT)
  395.     sT = Left$(sT, cT)
  396.     ExeNameFromMod = MUtility.GetFileBaseExt(sT)
  397. End Function
  398.  
  399. Function ModFromWnd(ByVal hWnd As Long) As Long
  400.     BugAssert hWnd <> hNull
  401.     ModFromWnd = ModFromProcID(MWinTool.ProcIDFromWnd(hWnd))
  402. End Function
  403.  
  404. Function ModFromProcID(ByVal idProc As Long) As Long
  405.     If Not MUtility.IsNT Then
  406.         Dim process As PROCESSENTRY32, module As MODULEENTRY32
  407.         Dim hSnap As Long, f As Long, idModule As Long
  408.         hSnap = CreateToolhelp32Snapshot(TH32CS_SNAPPROCESS, 0)
  409.         If hSnap = hNull Then Exit Function
  410.         ' Loop through to find matching process
  411.         process.dwSize = Len(process)
  412.         f = Process32First(hSnap, process)
  413.         Do While f
  414.             If process.th32ProcessID = idProc Then
  415.                 ' Save module ID
  416.                 idModule = process.th32ModuleID
  417.                 Exit Do
  418.             End If
  419.             f = Process32Next(hSnap, process)
  420.         Loop
  421.         
  422.         hSnap = CreateToolhelp32Snapshot(TH32CS_SNAPMODULE, idProc)
  423.         If hSnap = hNull Then Exit Function
  424.         ' Loop through to find matching module
  425.         module.dwSize = Len(module)
  426.         f = Module32First(hSnap, module)
  427.         Do While f
  428.             If module.th32ModuleID = idModule Then
  429.                 ModFromProcID = module.hModule
  430.                 Exit Function
  431.             End If
  432.             f = Module32Next(hSnap, module)
  433.         Loop
  434.     Else
  435.         Dim hModule As Long, c As Long
  436.         ' First module is the main executable
  437.         f = EnumProcessModules(ProcFromProcID(idProc), hModule, 4, c)
  438.         ' Ignore errors (probably you have no security access)
  439.         If f Then ModFromProcID = hModule
  440.     End If
  441. End Function
  442.  
  443. Function InstFromProcID(ByVal idProc As Long) As String
  444.     Dim f As Long, hModule As Long, c As Long
  445.     If Not MUtility.IsNT Then
  446.         Dim process As PROCESSENTRY32, module As MODULEENTRY32
  447.         Dim hSnap As Long, idModule As Long
  448.         hSnap = CreateToolhelp32Snapshot(TH32CS_SNAPPROCESS, 0)
  449.         If hSnap = hNull Then Exit Function
  450.         ' Loop through to find matching process
  451.         process.dwSize = Len(process)
  452.         f = Process32First(hSnap, process)
  453.         Do While f
  454.             If process.th32ProcessID = idProc Then
  455.                 ' Save module ID
  456.                 idModule = process.th32ModuleID
  457.                 Exit Do
  458.             End If
  459.             f = Process32Next(hSnap, process)
  460.         Loop
  461.         
  462.         ' Loop through modules
  463.         hSnap = CreateToolhelp32Snapshot(TH32CS_SNAPMODULE, idProc)
  464.         If hSnap = hNull Then Exit Function
  465.         module.dwSize = Len(module)
  466.         f = Module32First(hSnap, module)
  467.         Do While f
  468.             If module.th32ModuleID = idModule Then
  469.                 InstFromProcID = module.modBaseAddr
  470.                 Exit Function
  471.             End If
  472.             f = Module32Next(hSnap, module)
  473.         Loop
  474.     Else
  475.         ' First module is the main executable
  476.         f = EnumProcessModules(ProcFromProcID(idProc), hModule, 4, c)
  477.         If f = 0 Then Exit Function
  478.         Dim modinfo As MODULEINFO
  479.         f = GetModuleInformation(ProcFromProcID(idProc), hModule, modinfo, c)
  480.         If f Then InstFromProcID = modinfo.lpBaseOfDll
  481.     End If
  482. End Function
  483.  
  484. Function ProcIDFromInst(ByVal hInst As Long) As String
  485.     Dim f As Long, c As Long, idProc As Long
  486.     If Not MUtility.IsNT Then
  487.         Dim process As PROCESSENTRY32, hSnap As Long
  488.         hSnap = CreateToolhelp32Snapshot(TH32CS_SNAPPROCESS, 0)
  489.         If hSnap = hNull Then Exit Function
  490.         process.dwSize = Len(process)
  491.         f = Process32First(hSnap, process)
  492.         Do While f
  493.             If InstFromProcID(process.th32ProcessID) = hInst Then
  494.                 ProcIDFromInst = process.th32ProcessID
  495.                 Exit Function
  496.             End If
  497.             f = Process32Next(hSnap, process)
  498.         Loop
  499.     Else
  500.         Dim i As Long, iCur As Long, cRequest As Long, cGot As Long, modinfo As MODULEINFO
  501.         Dim aProcesses() As Long, hProcess As Long, hModule As Long
  502.         cRequest = 96       ' Request in bytes (32 processes)
  503.         Do
  504.             ReDim aProcesses(0 To (cRequest / 4) - 1) As Long
  505.             f = EnumProcesses(aProcesses(0), cRequest, cGot)
  506.             If f = 0 Then Exit Function
  507.             If cGot < cRequest Then Exit Do
  508.             cRequest = cRequest * 2
  509.         Loop
  510.         cGot = cGot / 4     ' From bytes to processes
  511.         ReDim Preserve aProcesses(0 To cGot - 1) As Long
  512.         
  513.         For i = 0 To cGot - 1
  514.             hProcess = OpenProcess(PROCESS_QUERY_INFORMATION Or _
  515.                                    PROCESS_VM_READ, 0, aProcesses(i))
  516.             ' Ignore processes that fail (probably don't have security rights)
  517.             If hProcess = 0 Then GoTo NextFor
  518.             ' Get first module only
  519.             f = EnumProcessModules(hProcess, hModule, 4, c)
  520.             If f = 0 Then GoTo NextFor
  521.             f = GetModuleInformation(ProcFromProcID(idProc), hModule, modinfo, c)
  522.             If f = 0 Then GoTo NextFor
  523.             ProcIDFromInst = modinfo.lpBaseOfDll
  524.             iCur = iCur + 1
  525. NextFor:
  526.         Next
  527.     End If
  528. End Function
  529.  
  530. Function ProcFromInst(ByVal hInst As Long) As String
  531.     ProcFromInst = ProcIDFromInst(hInst)
  532. End Function
  533.  
  534. Function ModFromInst(ByVal hInst As Long) As String
  535.     ModFromInst = ModFromProcID(ProcIDFromInst(hInst))
  536. End Function
  537.  
  538. Function ProcFromProcID(idProc As Long)
  539.     ProcFromProcID = OpenProcess(PROCESS_QUERY_INFORMATION Or _
  540.                                  PROCESS_VM_READ, 0, idProc)
  541. End Function
  542.  
  543. Function ExeNameFromWnd(ByVal hWnd As Long) As String
  544.     BugAssert hWnd <> hNull
  545.     ExeNameFromWnd = MUtility.GetFileBaseExt(ExePathFromWnd(hWnd))
  546. End Function
  547.  
  548. Function ExePathFromWnd(ByVal hWnd As Long) As String
  549.     ExePathFromWnd = ExePathFromProcID(MWinTool.ProcIDFromWnd(hWnd))
  550. End Function
  551.  
  552. Function ExePathFromProcID(idProc As Long) As String
  553.     If Not MUtility.IsNT Then
  554.         Dim process As PROCESSENTRY32, hSnap As Long, f As Long
  555.         hSnap = CreateToolhelp32Snapshot(TH32CS_SNAPPROCESS, 0)
  556.         If hSnap = hNull Then Exit Function
  557.         process.dwSize = Len(process)
  558.         f = Process32First(hSnap, process)
  559.         Do While f
  560.             If process.th32ProcessID = idProc Then
  561.                 ExePathFromProcID = MUtility.StrZToStr(process.szExeFile)
  562.                 Exit Function
  563.             End If
  564.             f = Process32Next(hSnap, process)
  565.         Loop
  566.     Else
  567.         Dim s As String, c As Long
  568.         s = String$(cMaxPath, 0)
  569.         c = GetModuleFileNameEx(ProcFromProcID(idProc), _
  570.                                 ModFromProcID(idProc), s, cMaxPath)
  571.         If c Then ExePathFromProcID = Left$(s, c)
  572.     End If
  573. End Function
  574.  
  575. Function ExeNameFromProcID(idProc As Long) As String
  576.     ExeNameFromProcID = MUtility.GetFileBaseExt(ExePathFromProcID(idProc))
  577. End Function
  578.  
  579. Function ModFromExePath(sExe As String) As Long
  580.     ModFromExePath = GetModuleHandle(sExe)
  581. End Function
  582.  
  583. Function GetFirstInstWnd(hWndMe As Long) As Long
  584.     Dim hWndYou As Long, idMe As Long, sExeMe As String
  585.     
  586.     ' Get my own process ID and executable name
  587.     idMe = MWinTool.ProcIDFromWnd(hWndMe)
  588.     sExeMe = ExeNameFromWnd(hWndMe)
  589.     ' Get first sibling to start iterating top-level windows
  590.     hWndYou = GetWindow(hWndMe, GW_HWNDFIRST)
  591.     Do While hWndYou <> hNull
  592.         ' Ignore if process ID of target is same
  593.         If idMe <> MWinTool.ProcIDFromWnd(hWndYou) Then
  594.             ' Ignore if module name is different
  595.             If sExeMe = ExeNameFromWnd(hWndYou) Then
  596.                 ' Return first with same module, different process
  597.                 GetFirstInstWnd = hWndYou
  598.                 Exit Function
  599.             End If
  600.         End If
  601.         ' Get next sibling
  602.         hWndYou = GetWindow(hWndYou, GW_HWNDNEXT)
  603.     Loop
  604. End Function
  605.  
  606. Function GetAllInstWnd(hWndMe As Long) As CVector
  607.     Dim hWndYou As Long, idMe As Long, sExeMe As String
  608.     Dim vecWnds As CVector, i As Long
  609.     Set vecWnds = New CVector
  610.     
  611.     ' Get my own process ID and executable name
  612.     idMe = MWinTool.ProcIDFromWnd(hWndMe)
  613.     sExeMe = ExeNameFromWnd(hWndMe)
  614.     ' Get first sibling to start iterating top level windows
  615.     hWndYou = GetWindow(hWndMe, GW_HWNDFIRST)
  616.     Do While hWndYou <> hNull
  617.         ' Ignore if process ID of target is same
  618.         If idMe <> MWinTool.ProcIDFromWnd(hWndYou) Then
  619.             ' Ignore if module name is different
  620.             If sExeMe = ExeNameFromWnd(hWndYou) Then
  621.                 ' Return all with same module, different process
  622.                 i = i + 1
  623.                 vecWnds(i) = hWndYou
  624.             End If
  625.         End If
  626.         ' Get next sibling
  627.         hWndYou = GetWindow(hWndYou, GW_HWNDNEXT)
  628.     Loop
  629.     Set GetAllInstWnd = vecWnds
  630. End Function
  631. '
  632.  
  633. #If fComponent = 0 Then
  634. Private Sub ErrRaise(e As Long)
  635.     Dim sText As String, sSource As String
  636.     If e > 1000 Then
  637.         sSource = App.ExeName & ".ModTool"
  638.         Select Case e
  639.         Case eeBaseModTool
  640.             BugAssert True
  641.        ' Case ee...
  642.        '     Add additional errors
  643.         End Select
  644.         Err.Raise COMError(e), sSource, sText
  645.     Else
  646.         ' Raise standard Visual Basic error
  647.         sSource = App.ExeName & ".VBError"
  648.         Err.Raise e, sSource
  649.     End If
  650. End Sub
  651. #End If
  652.  
  653.